GetNSEfloat Function

public function GetNSEfloat(grid1, grid2, maskReal, maskInteger, normalized) result(nash)

compute Nash and Sutcliffe efficiency index, equivalent to coefficient of determination. optional argument: mask: compute RMSE only on assigned mask nrmse: compute normalized Nash efficiency


References:
Nash, J. E. and J. V. Sutcliffe (1970), River flow forecasting through conceptual models part I — A discussion of principles, Journal of Hydrology, 10 (3), 282–290.

Moriasi, D. N.; Arnold, J. G.; Van Liew, M. W.; Bingner,R. L.; Harmel, R. D.; Veith, T. L. (2007), "Model Evaluation Guidelines for Systematic Quantification of Accuracy in Watershed Simulations", Transactions of the ASABE, 50 (3), 885–900. http://swat.tamu.edu/media/1312/moriasimodeleval.pdf

Nossent, J., Bauwens, W., Application of a normalized Nash-Sutcliffe efficiency to improve the accuracy of the Sobol’ sensitivity analysis of a hydrological model Geophysical Research Abstracts Vol. 14, EGU2012-237, 2012 EGU General Assembly 2012

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: grid1
type(grid_real), intent(in) :: grid2
type(grid_real), intent(in), optional :: maskReal
type(grid_integer), intent(in), optional :: maskInteger
logical, intent(in), optional :: normalized

Return Value real(kind=float)


Variables

Type Visibility Attributes Name Initial
integer(kind=long), public :: i
integer(kind=long), public :: j
real(kind=float), public :: meanobs
real(kind=float), public :: nashden
real(kind=float), public :: nashnum

Source Code

FUNCTION GetNSEfloat &
!
(grid1, grid2, maskReal, maskInteger, normalized) &
!
RESULT (nash)

IMPLICIT NONE

!Arguments with intent(in):
TYPE (grid_real), INTENT(IN) :: grid1  !modeled
TYPE (grid_real), INTENT(IN) :: grid2  !observation
TYPE (grid_real), OPTIONAL,  INTENT(IN) :: maskReal
TYPE (grid_integer), OPTIONAL,  INTENT(IN) :: maskInteger
LOGICAL, OPTIONAL, INTENT(IN) :: normalized


!Local declarations:
INTEGER (KIND = long) :: i, j
REAL (KIND = float) :: nash, meanobs, nashnum, nashden
!---------------------------end of declarations--------------------------------

nash = 0.
nashnum = 0.
nashden = 0.

!check grid1 and grid2 have the same coordinate reference system
 IF ( .NOT. CRSisEqual(grid1,grid2) ) THEN
      CALL Catch ('error', 'GridStatistics',  &
      'calculate NSE: ', argument = &
      'coordinate reference system of grid1 differs from grid2' )
END IF

IF (PRESENT (maskReal)) THEN
    IF ( .NOT. CRSisEqual(maskReal,grid1) ) THEN
        CALL Catch ('error', 'GridStatistics',  &
        'calculate NSE: ', argument = &
        'coordinate reference system of mask differs from input grid' )
    END IF
    
    !get mean of observations
     meanobs = GetMean (grid2, maskReal = maskReal)
    
    !compute numerator and denominator
    DO j = 1, maskReal % jdim
        DO i = 1, maskReal % idim
            IF (maskReal % mat(i,j) /= maskReal % nodata) THEN
                nashnum = nash + ( grid1 % mat (i,j) - grid2 % mat (i,j) ) **2.
                nashden = nashden + ( grid2 % mat (i,j) - meanobs ) **2.
            END IF
        END DO
    END DO
    
ELSE IF (PRESENT (maskInteger)) THEN
    IF ( .NOT. CRSisEqual(maskInteger,grid1) ) THEN
        CALL Catch ('error', 'GridStatistics',  &
        'calculate RMSE: ', argument = &
        'coordinate reference system of mask differs from input grid' )
    END IF

    !get mean of observations
     meanobs = GetMean (grid2, maskReal = maskReal)
    
    !compute numerator and denominator
    DO j = 1, maskInteger % jdim
        DO i = 1, maskInteger % idim
            IF (maskInteger % mat(i,j) /= maskInteger % nodata) THEN
                 nashnum = nashnum + ( grid1 % mat (i,j) - grid2 % mat (i,j) ) **2.
                 nashden = nashden + ( grid2 % mat (i,j) - meanobs ) **2.
            END IF
        END DO
    END DO

ELSE
   
    !get mean of observations
     meanobs = GetMean (grid2, maskReal = maskReal)
    
    !compute numerator and denominator
    DO j = 1, grid1 % jdim
        DO i = 1, grid1 % idim
            IF (grid1 % mat(i,j) /= grid1 % nodata) THEN
                 nashnum = nashnum + ( grid1 % mat (i,j) - grid2 % mat (i,j) ) **2.
                 nashden = nashden + ( grid2 % mat (i,j) - meanobs ) **2.
            END IF
        END DO
    END DO
END IF

IF (nashden /= 0.) THEN
   nash = 1. - nashnum / nashden
ELSE
   nash = -9999.9
END IF

IF (PRESENT(normalized)) THEN
  IF (normalized) THEN
    IF (nash == -9999.9) THEN
      nash = -9999.9
    ELSE
      nash = 1. / (2. - nash)
    END IF
  END IF
END IF

RETURN

END FUNCTION GetNSEfloat